CheckSpecificProperties Subroutine

public subroutine CheckSpecificProperties(model, ini)

check properties for each ET model

Arguments

Type IntentOptional Attributes Name
integer(kind=short), intent(in) :: model
type(IniList), intent(in) :: ini

Source Code

SUBROUTINE CheckSpecificProperties &
!
( model, ini )

IMPLICIT NONE

!Arguments with intent(in):
INTEGER (KIND = short), INTENT(in) :: model
TYPE (IniList)        , INTENT(in) :: ini

!----------------------------end of declarations-------------------------------

!check data specific for each ET model
SELECT CASE (model)
   CASE ( PENMAN_MONTEITH ) 
      IF ( dtTemperature <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires air temperature' )
      END IF
      
      IF ( dtRelHumidity <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires air relative humidity' )
      END IF
      
      IF ( dtWindSpeed <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires wind speed' )
      END IF
      
      IF ( dtRadiation <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires net radiation' )
      END IF
      
      IF ( .NOT. fvcoverLoaded ) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires vegetation fraction coverage' )
      END IF
      
      IF ( .NOT. laiLoaded ) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires leaf area index' )
      END IF
      
      IF ( .NOT. dem_loaded ) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires digital elevation model' )
      END IF
      
      IF ( .NOT. rsMinloaded ) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires minimum stomatal resistance' )
      END IF
      
      
   CASE ( FAO56_PENMAN_MONTEITH ) 
      IF ( dtTemperature <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires air temperature' )
      END IF
      
      IF ( dtRelHumidity <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires air relative humidity' )
      END IF
      
      IF ( dtWindSpeed <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires wind speed' )
      END IF
      
      IF ( dtRadiation <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires net radiation' )
      END IF
      
      IF ( .NOT. fvcoverLoaded ) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires vegetation fraction coverage' )
      END IF
      
      
      IF ( .NOT. dem_loaded ) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires digital elevation model' )
      END IF
      
      
   CASE (PRIESTLEY_TAYLOR) 
       IF ( dtTemperature <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires air temperature' )
      END IF
      
      IF ( dtRadiation <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires net radiation' )
      END IF
      
      IF ( .NOT. fvcoverLoaded ) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires vegetation fraction coverage' )
      END IF
      
      IF ( .NOT. dem_loaded ) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires digital elevation model' )
      END IF
      
      !IF ( .NOT. plantsHeightLoaded ) THEN
      !     CALL Catch ('error', 'Evapotranspiration',   &
      !          'ET model requires vegetation height' )
      !END IF
 
   CASE (HARGREAVES) 
       
       compute_hargreaves = .TRUE.
      
       
      IF ( dtET /= day ) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires daily dt' ) 
      END IF
       
      IF ( dtTemperatureDailyMean <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires daily air temperature' )
      END IF
      
      IF ( dtTemperatureDailyMin <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires daily minimum air temperature' )
      END IF
      
      IF ( dtTemperatureDailyMax <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires daily maximum air temperature' )
      END IF
      
   CASE (HARGREAVES_MOD) 
      
      compute_hargreaves = .TRUE. 
       
      IF ( dtET /= day ) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires daily dt' ) 
      END IF
       
      IF ( dtTemperatureDailyMean <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires daily air temperature' )
      END IF
      
      IF ( dtTemperatureDailyMin <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires daily minimum air temperature' )
      END IF
      
      IF ( dtTemperatureDailyMax <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires daily maximum air temperature' )
      END IF
      
      IF ( .NOT. dem_loaded ) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires digital elevation model' )
      END IF
      
      
      
        
   CASE (ENERGY_BALANCE)
       
       IF ( dtTemperature <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires air temperature' )
      END IF
      
      IF ( dtRelHumidity <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires air relative humidity' )
      END IF
      
      IF ( dtWindSpeed <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires wind speed' )
      END IF
      
      IF ( dtRadiation <= 0) THEN
          CALL Catch ('error', 'Evapotranspiration',   &
                'ET model requires net radiation' )
      END IF
      
	
END SELECT


RETURN
END SUBROUTINE CheckSpecificProperties